home *** CD-ROM | disk | FTP | other *** search
/ Libris Britannia 4 / science library(b).zip / science library(b) / CUGUK / COMMS / C101.ZIP / UUPC11XS.ZIP / UUCICO / COMMFIFO.ASM < prev    next >
Assembly Source File  |  1992-12-18  |  50KB  |  1,617 lines

  1.     TITLE    COMM
  2.     PAGE    83,132
  3. ;    $Id: COMMFIFO.ASM 1.2 1992/12/18 12:08:25 ahd Exp $
  4. ;
  5. ;    $Log: COMMFIFO.ASM $
  6. ;; Revision 1.2  1992/12/18  12:08:25  ahd
  7. ;; Add Plummer's fix for bad TASM assemble of com_errors
  8. ;;
  9. ;
  10. ;  2-Dec-92 plummer    Fix com_errors() again.  Change got lost.
  11. ; Fix com_errors() to avoid problems with tasm.  Plummer, 11/16/92
  12. ; 8259 EOI issued after interrupts serviced.  Plummer, 3/25/92
  13. ; Fix botch in Set_Baud.  Plummer, 3/20/92
  14. ; Put in Gordon Lee's cure from dropped interrupts.  Plummer, 3/19/92
  15. ; TEMPORARY ioctl_com().  Plummer, 3/9/92.
  16. ; Clear OUT2 bit in UART.  Some machines use it so enable IRQ. Plummer, 3/9/92
  17. ; Release send buffer if we can't assign a recv buffer.  Plummer, 3/9/92
  18. ; Move EQU's outside of SP_TAB struc definition.  ahd, 3/8/92.
  19. ; ahd changes: short jmp's out of range in INST, OPEN ???  (ahd, 3/?/92)
  20. ; open_com() leaves DTR unchanged so Drew's autobaud works.  Plummer, 3/2/92
  21. ; Missing DX load in close_com() -- FIFO mode not cleared.  Plummer, 3/2/92
  22. ; C calling convention does not require saving AX, BX, CX, DX. Plummer 2/23/92
  23. ; Flush consideration of the PC Jr.  Wm. W. Plummer, 2/15/92
  24. ; Cleanup PUSHF/POPF and CLI/STI useage.  Wm. W. Plummer, 2/15/92
  25. ; Make SENDII have Giles Todd's change.  Wm. W. Plummer, 2/15/92
  26. ; Changes to Giles Todd's code to support dynamic buffers.  Plummer, 2/3/92
  27. ; 26 Jan 92 Giles Todd    Prime THR for UARTs which do not give a Tx empty
  28. ;            interrupt when Tx interrupts are enabled.
  29. ; S_SIZE & R_SIZE may be set with -D to MASM.  Wm. W. Plummer, 1/19/92
  30. ; Assign buffers dynamically.  Wm. W. Plummer, 1/19/92
  31. ; Unfix byte length -- I screwed up.  Wm. W. Plummer, 1/15/92
  32. ; Fix byte length with specific PARITY select.    Wm. W. Plummer, 1/13/92
  33. ; Buffers up to 4096 per AHD.  Wm. W. Plummer, 1/1/92
  34. ; Always use FIFO length of 16 on send side.  Wm. W. Plummer, 12/30/91.
  35. ; Init DSR and CTS previous state from current status.    Wm. Plummer, 12/30/91.
  36. ; UUPC conditional to disable v.24.  Wm. W. Plummer, 12/30/91.
  37. ; Buffer sizes up to 2048 per ahd.  Wm. W. Plummer, 12/15/91.
  38. ; dtr_on() switches to D connection if CTS&DSR don't come up.  WWP, 12/15/91.
  39. ; New dtr_on() logic.  Wm. W. Plummer, 12/11/91
  40. ; Fix bad reg. per report from user.  Wm. W. Plummer, 12/11/91
  41. ; Semicolon before control-L's for MASM 5.00 per ahd. Wm. W. Plummer, 12/8/91
  42. ; Use AHD's handling of COM ports.  Wm. W. Plummer, 11/29/91
  43. ; Buffer sizes reduced and required to be 2**N.  Wm. W. Plummer, 11/11/91
  44. ; Accomodate V.24 requirements on DTR flaps.  Wm. W. Plummer 10/15/91
  45. ; Revised DTR_ON_COM to solve user problem.  Wm. W. Plummer, 10/3/91
  46. ; Make time delays independent of CPU speed.  Wm. W. Plummer, 9/16/91
  47. ; Use interrupts to trace CD, DSR, Wm. W. Plummer, 9/16/91
  48. ; Remove modem control from TXI. Wm. W. Plummer, 9/13/91
  49. ; Completely redo the XOFF/XON logic.  Too many races before. Wm. W. Plummer
  50. ; Revise interrupt dispatch for speed & function.  William W. Plummer, 9/12/91
  51. ; Merge in ahd's changes to flush control Q,S when received as flow control
  52. ; SEND buffer allows one byte for a SENDII call.  Avoids flow control
  53. ;  lockups. - William W. Plummer, 8/30/91
  54. ; Support for NS16550A chip with SILO - William W. Plummer, 8/30/91
  55. ; Add modem_status() routine - William W. Plummer, 7/2/91
  56. ; Put wrong code under AHD conditional - William W. Plummer, 7/2/91
  57. ; Change TITLE, repair bad instr after INST3 - William W. Plummer, 7/1/91
  58. ; Modified to use COM1 thru COM4 - William W. Plummer, 2/21/91
  59. ; Eliminate (incomplete) support for DOS1 - William W. Plummer, 11/13/90
  60.  
  61. ; Changes may be copied and modified with no notice.  Copyrights and copylefts
  62. ; are consider silly and do not apply.    --  William W. Plummer
  63.  
  64. ; modified to use MSC calling sequence.  jrr 3/86
  65. ;****************************************************************************
  66. ; Communications Package for the IBM PC, XT, AT and strict compatibles.
  67. ; May be copied and used freely -- This is a public domain program
  68. ; Developed by Richard Gillmann, John Romkey, Jerry Saltzer,
  69. ; Craig Milo Rogers, Dave Mitton and Larry Afrin.
  70. ;
  71. ; We'd sure like to see any improvements you might make.
  72. ; Please send all comments and queries about this package
  73. ; to GILLMANN@USC-ISIB.ARPA
  74. ;
  75. ; o Supports both serial ports simultaneously
  76. ; o All speeds to 19200 baud
  77. ; o Compatible with PC, XT, AT
  78. ; o Built in XON/XOFF flow control option
  79. ; o C language calling conventions
  80. ; o Logs all comm errors
  81. ; o Direct connect or modem protocol
  82.     PAGE;
  83. ;
  84. ; Buffer sizes -- *** MUST be powers of 2 ****
  85.  
  86. IFDEF UUPC
  87.     R_SIZE    EQU    4096
  88.     S_SIZE    EQU    4096
  89. ENDIF
  90.  
  91. ; If not set above, maybe on assembler command line.  But if not, ...
  92. IFNDEF R_SIZE
  93.     R_SIZE    EQU    512    ; Recv buffer size
  94. ENDIF
  95. IFNDEF S_SIZE
  96.     S_SIZE    EQU    512    ; Send buffer size
  97. ENDIF
  98.  
  99. ; INTERRUPT NUMBERS
  100. INT_COM1 EQU    0CH        ; COM1: FROM 8259
  101. INT_COM2 EQU    0BH        ; COM2: FROM 8259
  102. INT_COM3 EQU    0CH        ; COM3: FROM 8259
  103. INT_COM4 EQU    0BH        ; COM4: FROM 8259
  104. ; 8259 PORTS
  105. INTA00    EQU    20H        ; 8259A PORT, A0 = 0
  106. INTA01    EQU    21H        ; 8259A PORT, A0 = 1
  107. ; COM1: & COM3: LEVEL 4
  108. IRQ4    EQU    2*2*2*2     ; 8259A OCW1 MASK, M4=1, A0=0
  109. NIRQ4    EQU    NOT IRQ4 AND 0FFH ; COMPLEMENT OF ABOVE
  110. EOI4    EQU    4 OR 01100000B    ; 8259A OCW2 SPECIFIC IRQ4 EOI, A0=0
  111. ; COM2: & COM4: LEVEL 3
  112. IRQ3    EQU    2*2*2        ; 8259A OCW1 MASK, M3=1, A0=0
  113. NIRQ3    EQU    NOT IRQ3 AND 0FFH ; COMPLEMENT OF ABOVE
  114. EOI3    EQU    3 OR 01100000B    ; 8259A OCW2 SPECIFIC IRQ3 EOI, A0=0
  115.  
  116. ; FLOW CONTROL CHARACTERS
  117. CONTROL_Q EQU    11H        ; XON
  118. CONTROL_S EQU    13H        ; XOFF
  119. ; MISC.
  120. DOS    EQU    21H        ; DOS FUNCTION CALLS
  121.  
  122. ;
  123. ; ROM BIOS Data Area
  124. ;
  125. RBDA    SEGMENT AT 40H
  126. RS232_BASE DW    4 DUP(?)    ; ADDRESSES OF RS232 ADAPTERS
  127. RBDA    ENDS
  128.     PAGE;
  129. ;
  130. ; TABLE FOR EACH SERIAL PORT
  131. ;
  132. SP_TAB        STRUC
  133. PORT        DB    ?    ; 1 OR 2 OR 3 OR 4
  134. ; PARAMETERS FOR THIS INTERRUPT LEVEL
  135. INT_COM     DB    ?    ; INTERRUPT NUMBER
  136. IRQ        DB    ?    ; 8259A OCW1 MASK
  137. NIRQ        DB    ?    ; COMPLEMENT OF ABOVE
  138. EOI        DB    ?    ; 8259A OCW2 SPECIFIC END OF INTERRUPT
  139. ; INTERRUPT HANDLERS FOR THIS LEVEL
  140. INT_HNDLR    DW    ?    ; OFFSET TO INTERRUPT HANDLER
  141. OLD_COM_OFF    DW    ?    ; OLD HANDLER'S OFFSET
  142. OLD_COM_SEG    DW    ?    ; OLD HANDLER'S SEGMENT
  143. ; ATTRIBUTES
  144. INSTALLED    DB    ?    ; IS PORT INSTALLED ON THIS PC? (1=YES,0=NO)
  145. BAUD_RATE    DW    ?    ; 19200 MAX
  146. CONNECTION    DB    ?    ; M(ODEM), D(IRECT)
  147. PARITY        DB    ?    ; N(ONE), O(DD), E(VEN), S(PACE), M(ARK)
  148. STOP_BITS    DB    ?    ; 1, 2
  149. XON_XOFF    DB    ?    ; E(NABLED), D(ISABLED)
  150. ; FLOW CONTROL STATE
  151. HOST_OFF    DB    ?    ; HOST XOFF'ED (1=YES,0=NO)
  152. PC_OFF        DB    ?    ; PC XOFF'ED (1=YES,0=NO)
  153. URGENT_SEND    DB    ?    ; We MUST send one byte (XON/XOFF)
  154. SEND_OK     DB    ?    ; DSR and CTS are ON
  155. ; ERROR COUNTS
  156. ERROR_BLOCK    DW    8 DUP(?); EIGHT ERROR COUNTERS
  157.  
  158. ; UART PORTS - DATREG thru MSR must be in order shown.
  159. DATREG        DW    ?    ; DATA REGISTER
  160. IER        DW    ?    ; INTERRUPT ENABLE REGISTER
  161. IIR        DW    ?    ; INTERRUPT IDENTIFICATION REGISTER (RO)
  162. LCR        DW    ?    ; LINE CONTROL REGISTER
  163. MCR        DW    ?    ; MODEM CONTROL REGISTER
  164. LSR        DW    ?    ; LINE STATUS REGISTER
  165. MSR        DW    ?    ; MODEM STATUS REGISTER
  166. UART_SILO_LEN    DB    ?    ; Size of a silo chunk (1 for 8250)
  167. ;
  168. ; BUFFER POINTERS
  169. START_TDATA    DW    ?    ; INDEX TO FIRST CHARACTER IN X-MIT BUFFER
  170. END_TDATA    DW    ?    ; INDEX TO FIRST FREE SPACE IN X-MIT BUFFER
  171. START_RDATA    DW    ?    ; INDEX TO FIRST CHARACTER IN REC. BUFFER
  172. END_RDATA    DW    ?    ; INDEX TO FIRST FREE SPACE IN REC. BUFFER
  173. ; BUFFER COUNTS
  174. SIZE_TDATA    DW    ?    ; NUMBER OF CHARACTERS IN X-MIT BUFFER
  175. SIZE_RDATA    DW    ?    ; NUMBER OF CHARACTERS IN REC. BUFFER
  176. ; BUFFERS
  177. TBuff        DD    ?    ; Pointer to transmit buffer
  178. RBuff        DD    ?    ; Pointer to receive buffer
  179. SP_TAB        ENDS
  180.  
  181. ; SP_TAB EQUATES
  182. ; WE HAVE TO USE THESE BECAUSE OF PROBLEMS WITH STRUC
  183. EOVFLOW  EQU    ERROR_BLOCK    ; BUFFER OVERFLOWS
  184. EOVRUN        EQU    ERROR_BLOCK+2    ; RECEIVE OVERRUNS
  185. EBREAK        EQU    ERROR_BLOCK+4    ; BREAK CHARS
  186. EFRAME        EQU    ERROR_BLOCK+6    ; FRAMING ERRORS
  187. EPARITY  EQU    ERROR_BLOCK+8        ; PARITY ERRORS
  188. EXMIT        EQU    ERROR_BLOCK+10    ; TRANSMISSION ERRORS
  189. EDSR        EQU    ERROR_BLOCK+12    ; DATA SET READY ERRORS
  190. ECTS        EQU    ERROR_BLOCK+14    ; CLEAR TO SEND ERRORS
  191. DLL        EQU    DATREG        ; LOW DIVISOR LATCH
  192. DLH        EQU    IER        ; HIGH DIVISOR LATCH
  193.  
  194. ;
  195. ; Equates having to do with the FIFO
  196. ;
  197. FCR        EQU    IIR    ; FIFO Control Register (WO)
  198.  ; Bits in FCR for NS16550A UART.  Note that writes to FCR are ignored
  199.  ; by other chips.
  200.  FIFO_ENABLE    EQU    001H    ; Enable FIFO mode
  201.  FIFO_CLR_RCV    EQU    002H    ; Clear receive FIFO
  202.  FIFO_CLR_XMT    EQU    004H    ; Clear transmit FIFO
  203.  FIFO_STR_DMA    EQU    008H    ; Start DMA Mode
  204.  ; 10H and 20H bits are register bank select on some UARTs (not handled)
  205.  FIFO_SZ_4    EQU    040H    ; Warning level is 4 before end
  206.  FIFO_SZ_8    EQU    080H    ; Warning level is 8 before end
  207.  FIFO_SZ_14    EQU    0C0H    ; Warning level is 14 before end
  208.  ;
  209.  ; Commands used in code to operate FIFO.  Made up as combinations of above
  210.  ;
  211.  FIFO_CLEAR    EQU    0    ; Turn off FIFO
  212.  FIFO_SETUP    EQU    FIFO_SZ_14 OR FIFO_ENABLE
  213.  FIFO_INIT    EQU    FIFO_SETUP OR FIFO_CLR_RCV OR FIFO_CLR_XMT
  214.  ;
  215.  ; Miscellaneous FIFO-related stuff
  216.  ;
  217. FIFO_ENABLED    EQU    0C0H    ; 16550 makes these equal FIFO_ENABLE
  218. FIFO_LEN    EQU    16    ; Length of the FIFOs in a 16550A
  219.     PAGE;
  220. ;    put the data in the DGROUP segment
  221. ;    far calls enter with DS pointing to DGROUP
  222. ;
  223. DGROUP    GROUP _DATA
  224. _DATA    SEGMENT PUBLIC 'DATA'
  225. ;
  226. DIV50        DW    2304    ; ACTUAL DIVISOR FOR 50 BAUD IN USE
  227. CURRENT_AREA    DW    AREA1    ; CURRENTLY SELECTED AREA
  228. ; DATA AREAS FOR EACH PORT
  229. AREA1    SP_TAB    <1,INT_COM1,IRQ4,NIRQ4,EOI4>    ; COM1 DATA AREA
  230. AREA2    SP_TAB    <2,INT_COM2,IRQ3,NIRQ3,EOI3>    ; COM2 DATA AREA
  231. AREA3    SP_TAB    <3,INT_COM3,IRQ4,NIRQ4,EOI4>    ; COM3 DATA AREA
  232. AREA4    SP_TAB    <4,INT_COM4,IRQ3,NIRQ3,EOI3>    ; COM4 DATA AREA
  233. _DATA    ENDS
  234.  
  235.  
  236.  
  237.  
  238. COM_TEXT SEGMENT PARA PUBLIC 'CODE'
  239.      ASSUME CS:COM_TEXT,DS:DGROUP,ES:NOTHING
  240.  
  241.      PUBLIC AREA1, AREA2, AREA3, AREA4
  242.      PUBLIC _select_port
  243.      PUBLIC _save_com
  244.      PUBLIC _install_com
  245.      PUBLIC _restore_com
  246.      PUBLIC _open_com
  247.      PUBLIC _ioctl_com
  248.      PUBLIC _close_com
  249.      PUBLIC _dtr_on
  250.      PUBLIC _dtr_off
  251.      PUBLIC _r_count
  252.      PUBLIC _s_count
  253.      PUBLIC _receive_com
  254.      PUBLIC _send_com
  255.      PUBLIC _sendi_com
  256. IFNDEF UUPC
  257.      PUBLIC _send_local
  258. ENDIF
  259.      PUBLIC _break_com
  260.      PUBLIC _com_errors
  261.      PUBLIC _modem_status
  262. IFDEF DEBUG
  263.      PUBLIC INST2, INST4
  264.      PUBLIC OPEN1, OPEN2, OPENX
  265.      PUBLIC DTRON1, DTRON6, DTRONF, DTRONS, DTRONX
  266.      PUBLIC RECV1, RECV3, RECV4, RECVX
  267.      PUBLIC SEND1, SENDX
  268.      PUBLIC WaitN, WaitN1, WaitN2
  269.      PUBLIC SENDII, SENDII2, SENDII4, SENDIIX
  270.      PUBLIC CHROUT, CHROUX
  271.      PUBLIC BREAKX
  272.      PUBLIC INT_HNDLR1, INT_HNDLR2, INT_HNDLR3, INT_HNDLR4
  273.      PUBLIC INT_COMMON, REPOLL, INT_END
  274.      PUBLIC LSI
  275.      PUBLIC MSI
  276.      PUBLIC TXI, TXI1, TXI2, TXI3, TXI9
  277.      PUBLIC TX_CHR
  278.      PUBLIC RXI, RXI0, RXI1, RXI2, RXI6, RXIX
  279. ENDIF
  280.     PAGE;
  281. ; Notes, thoughts and explainations by Bill Plummer.  These are intended to
  282. ; help those of you who would like to make modifications.
  283.  
  284. ; Here's the order of calls in UUPC.  The routines in COMM.ASM are called
  285. ; from ulib.c.
  286.  
  287. ; First (when a line in system has been read?), ulib&openline calls
  288. ;     select_port()        ; Sets up CURRENT_AREA
  289. ; then,  save_com()        ; Save INT vector
  290. ; then,  install_com()        ; Init area, hook INT
  291. ; then,  open_com(&cmd, 'D', 'N', STOP*T, 'D')  ; Init UART, clr bufs
  292. ; then,  dtr_on().
  293.  
  294. ; At that point the line is up and running.  UUPC calls ulib&sread()
  295. ; which calls,    receive_com();
  296.  
  297. ; And UUPC calls ulib&swrite()
  298. ; which calls,    send_com();
  299.  
  300. ; To cause an error that the receiver will see, UUPC calls ulib&ssendbrk();
  301. ; which calls,    break_com();
  302.  
  303. ; When all done with the line, UUPC calls ulib&closeline()
  304. ; which calls,    dtr_off();
  305. ; then,  close_com();
  306. ; then,  restore_com();     ; Unhook INT
  307. ; and,     stat_errors();
  308.  
  309.  
  310. ; Note: On the PC COM1 and COM3 share IRQ4, while COM2 and COM4 share IRQ3.
  311. ; BUT, only one device on a given IRQ line can be active at a time.  So it is
  312. ; sufficient for UUPC to hook whatever IRQ INT its modem is on as long as it
  313. ; unhooks it when it is done with that COM port.  COMM cannot be an installed
  314. ; device driver since it must go away when UUPC is done so that other devices
  315. ; on the same INTs will come back to life.  Also, it is OK to have a static
  316. ; CURRENT_AREA containing the current area that UUPC is using.
  317.  
  318. ; Note about using the NS16550A UART chip's FIFOs.  These are operated as
  319. ; silos.  In other words when an interrupt happens because the receive(send)
  320. ; FIFO is nearly full(empty), as many bytes as possible are transferred and
  321. ; the interrupt dismissed.  Thus, the interrupt load is lowered.
  322.  
  323.  
  324. ; Concerning the way the comm line is brought up.
  325. ; There are two basic cases, the Direct ('D') connection and the Modem ('M')
  326. ; connection.  For either UUPC calls dtr_on_com() to bring up the line.  This
  327. ; causes Data Terminal Ready (DTR) and Request To Send (RTS) to be set.  Note
  328. ; this is OK for a simple 3-wire link but may be REQUIRED for a COM port
  329. ; connected to an external modem.
  330.  
  331. ; The difference between a D connection and an M connection is
  332. ; whether or not the PC can expect any signals back from the modem.  If
  333. ; there is a simple 3-wire link, Data Set Ready will be floating.
  334. ; (Actually, some wise people jumper Data Terminal Read back to Data
  335. ; Set Ready so the PC sees its own DTR appear as DSR.)    UUPC should be
  336. ; able to handle the simplest cable as a design feature.  So both D and
  337. ; M connections send out DTR and RTS, but only the M connection expects
  338. ; a modem to respond.
  339.  
  340. ; Then, if it is full modem connection (M), we wait for a few
  341. ; seconds hoping that both Data Set Ready (DSR) and Clear To Send (CTS)
  342. ; will come up.  If they don't, the associated counters are incremented
  343. ; for subsequent printing in the error log.  Note that no error is
  344. ; reported from COMM to UUPC at this point, although this would be a
  345. ; good idea.  COMMFIFO.ASM forces the connection to be a D type and lets
  346. ; UUPC storm ahead with its output trying to
  347. ; establish a link, but the output is never sent due to one of the
  348. ; control signals being false.    UUPC could check the modem status using
  349. ; a call which has been installed just for this purpose.
  350.  
  351. ; Note, if you are going to connect your PC running UUPC to,
  352. ; say, a mainframe and you need hardware flow control (i.e., RTS-CTS
  353. ; handshaking), use a Modem connection.  Using a simple 3-wire cable
  354. ; forbids hardware flow control and UUPC must be instructed to use a
  355. ; Direct connection.  Refer to comments in the SYSTEMS file on how to
  356. ; make this selection.
  357.  
  358. ; References used in designing the revisions to COMM.ASM:
  359. ;    1.    The UNIX fas.c Driver code.
  360. ;    2.    SLIP8250.ASM from the Clarkson driver set.
  361. ;    3.    NS16550A data sheet and AN-491 from National Semiconductor.
  362. ;    4.    Bell System Data Communications, Technical Reference for
  363. ;        Data Set 103A, Interface Specification, February, 1967
  364. ;    5.    Network mail regarding V.24
  365. ;    6.    Joe Doupnik
  366.     PAGE;
  367. ;
  368. ; void far select_port(int)
  369. ;    Arg is 1..4 and specifies which COM port is referenced by
  370. ;    all other calls in this package.
  371. ;
  372. _select_port PROC FAR
  373.     push bp
  374.     mov bp,sp
  375.     mov AX,[bp+6]            ; get aguement
  376.     CMP    AL,1            ; Port 1?
  377.      JE    SP1            ; Yes
  378.     CMP    AL,2            ; Port 2?
  379.      JE    SP2            ; Yes
  380.     CMP    AL,3            ; Port 3?
  381.      JE    SP3            ; Yes
  382.     CMP    AL,4            ; Port 4?
  383.      JE    SP4            ; Yes
  384.     INT 20H             ; N.O.T.A. ????? Halt for debugging!
  385.     ; Assume port 1 if continued
  386. SP1:    MOV    AX,OFFSET DGROUP:AREA1    ; SELECT COM1 DATA AREA
  387.     JMP    SHORT SPX        ; CONTINUE
  388. SP2:    MOV    AX,OFFSET DGROUP:AREA2    ; SELECT COM2 DATA AREA
  389.     JMP    SHORT SPX        ; CONTINUE
  390. SP3:    MOV    AX,OFFSET DGROUP:AREA3    ; SELECT COM3 DATA AREA
  391.     JMP    SHORT SPX        ; CONTINUE
  392. SP4:    MOV    AX,OFFSET DGROUP:AREA4    ; SELECT COM4 DATA AREA
  393.     ;Fall into SPX
  394. SPX:    MOV    CURRENT_AREA,AX     ; SET SELECTION IN MEMORY
  395.     mov sp,bp
  396.     pop bp
  397.     RET
  398. _select_port ENDP
  399.     PAGE;
  400. ;
  401. ; void far save_com(void)
  402. ;    Save the interrupt vector of the selected COM port.
  403. ;    N.B. save_com() and restore_com() call MUST be properly nested
  404. ;
  405. _save_com PROC FAR
  406.     push bp
  407.     mov bp,sp
  408.     PUSH SI
  409.     PUSH    ES            ; SAVE EXTRA SEGMENT
  410.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  411.     MOV    AREA1.INT_HNDLR,OFFSET INT_HNDLR1
  412.     MOV    AREA2.INT_HNDLR,OFFSET INT_HNDLR2
  413.     MOV    AREA3.INT_HNDLR,OFFSET INT_HNDLR3
  414.     MOV    AREA4.INT_HNDLR,OFFSET INT_HNDLR4
  415.  
  416. ; Save old interrupt vector
  417.     MOV    AH,35H            ; FETCH INTERRUPT VECTOR CONTENTS
  418.     MOV    AL,INT_COM[SI]        ; INTERRUPT NUMBER
  419.     INT    DOS            ; DOS 2 FUNCTION
  420.     MOV    OLD_COM_OFF[SI],BX    ; SAVE
  421.     MOV    BX,ES            ; ES:BX
  422.     MOV    OLD_COM_SEG[SI],BX    ; FOR LATER RESTORATION
  423.     POP    ES            ; RESTORE ES
  424.     POP SI
  425.     mov sp,bp
  426.     pop bp
  427.     RET                ; DONE
  428. _save_com ENDP
  429.     PAGE;
  430. ;
  431. ; int far install_com(void)
  432. ;
  433. ;    Install the selected COM port.
  434. ;    Returns:    0: Failure
  435. ;            1: Success
  436. ;
  437. ; SET UART PORTS FROM RS-232 BASE IN ROM BIOS DATA AREA
  438. ; INITIALIZE PORT CONSTANTS AND ERROR COUNTS
  439. ;
  440. ; Assign blocks of memory for transmit and receive buffers
  441. ;
  442. _install_com PROC FAR
  443.     push bp
  444.     mov bp,sp
  445.     PUSHF                ; Save caller's interrupt state
  446.     PUSH SI
  447.     PUSH DI
  448.     PUSH ES
  449.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  450.     CMP    INSTALLED[SI],1     ; Is port installed on this machine?
  451.      JNE    INST1            ; NO, CONTINUE
  452.     JMP    INST9            ; ELSE JUMP IF ALREADY INSTALLED
  453.  
  454. ; Assign memory for transmit and receive buffers
  455.  
  456. INST1:    MOV BX,S_SIZE            ; Send buffer size
  457.     ADD BX,0FH            ; Round up
  458.     SHR BX,1            ; Must run on an XT
  459.     SHR BX,1
  460.     SHR BX,1
  461.     SHR BX,1            ; Now have number of paragraphs
  462.     MOV AX,4800H            ; Allocate memory
  463.     INT DOS
  464.      JC INSTFAIL            ; Give fail return
  465.     MOV WORD PTR TBuff[SI],0    ; Save in private block for this port
  466.     MOV WORD PTR TBuff[SI+2],AX
  467.  
  468.     MOV BX,R_SIZE            ; Receive buffer size
  469.     ADD BX,0FH            ; Round up
  470.     SHR BX,1            ; Must run on an XT
  471.     SHR BX,1
  472.     SHR BX,1
  473.     SHR BX,1            ; Now have number of paragraphs
  474.     MOV AX,4800H            ; Allocate memory
  475.     INT DOS
  476.      JNC INSTSUCC            ; Success --> Continue
  477.  
  478.     ; Unhand the send buffer assigned above
  479.  
  480.     MOV AX,WORD PTR TBuff+2[SI]    ; Transmit buffer paragraph
  481.     MOV ES,AX            ; Honest.  That's where the arg goes.
  482.     MOV AX,4900H            ; Release memory
  483.     INT DOS
  484.     ; Ignore error
  485.     ; Fall into INSTFAIL
  486.  
  487. INSTFAIL:
  488.      JMP INST666            ; Failure --> Give failed response
  489.  
  490. INSTSUCC:
  491.     MOV WORD PTR RBuff[SI],0    ; Save in private block for this port
  492.     MOV WORD PTR RBuff[SI+2],AX
  493.  
  494. IFDEF DEBUG
  495.     PUSH DI
  496.     CLD                ; Go up in memory
  497.     XOR AX,AX            ; A zero to store
  498.     LES DI,TBuff[SI]        ; Transmit buffer location
  499.     MOV CX,S_SIZE            ; Size of buffer
  500.     REP STOSB            ; Clear entire buffer
  501.     LES DI,RBuff[SI]        ; Receive buffer location
  502.     MOV CX,R_SIZE            ; Size of buffer
  503.     REP STOSB            ; Clear entire buffer
  504.     POP DI
  505. ENDIF
  506.     PAGE;
  507.  
  508. ; CLEAR ERROR COUNTS
  509.     CLI                ; Stray interrupts cause havoc
  510.     MOV    WORD PTR EOVFLOW[SI],0    ; BUFFER OVERFLOWS
  511.     MOV    WORD PTR EOVRUN[SI],0    ; RECEIVE OVERRUNS
  512.     MOV    WORD PTR EBREAK[SI],0    ; BREAK CHARS
  513.     MOV    WORD PTR EFRAME[SI],0    ; FRAMING ERRORS
  514.     MOV    WORD PTR EPARITY[SI],0    ; PARITY ERRORS
  515.     MOV    WORD PTR EXMIT[SI],0    ; TRANSMISSION ERRORS
  516.     MOV    WORD PTR EDSR[SI],0    ; DATA SET READY ERRORS
  517.     MOV    WORD PTR ECTS[SI],0    ; CLEAR TO SEND ERRORS
  518.  
  519.     MOV    BX,RBDA         ; ROM BIOS DATA AREA
  520.     MOV    ES,BX            ; TO ES
  521.     ASSUME    ES:RBDA
  522.  
  523. ; Map port number (COMx) into IO Address using the RS232_Base[x] table in
  524. ; the BIOS data area.  If any of the ports is missing there should be a
  525. ; zero in the table for this COM port.    BIOS startup routines pack the table
  526. ; so that if you have a COM4 but no COM3, 2E8 will be found in 40:4 and 0
  527. ; will be in 40:6.
  528.  
  529. ; N.B. The exact IO address in 40:x is irrelevant and may well be something
  530. ; other than the "standard" values if specially designed hardware is used.
  531. ; To minimize flack, we will use the standard value if the slot in the table
  532. ; is 0.  The bad side effect of this is that (in the standard losing case of
  533. ; a COM4 but no COM3) both COM3 and COM4 will reference the hardware at 2E8.
  534.  
  535.     CMP    PORT[SI],1        ; PORT 1?
  536.      JE    INST3F8         ; Yes
  537.     CMP    PORT[SI],2        ; PORT 2?
  538.      JE    INST2F8         ; Yes
  539.     CMP    PORT[SI],3        ; PORT 3?
  540.      JE    INST3E8         ; Yes
  541.     CMP    PORT[SI],4        ; PORT 4?
  542.      JE    INST2E8         ; Yes
  543.     INT    20H            ; NOTA. (Caller is screwed up badly)
  544.  
  545. INST3F8:MOV AX,3F8H            ; Standard COM1 location
  546.     CMP    RS232_BASE+0,0000H    ; We have information?
  547.      JE    INST2            ; No --> Use default
  548.     MOV    AX,RS232_BASE+0     ; Yes --> Use provided info
  549.     JMP    SHORT INST2        ; CONTINUE
  550.  
  551. INST2F8:MOV AX,2F8H            ; Standard COM2 location
  552.     CMP    RS232_BASE+2,0000H    ; We have information?
  553.      JE    INST2            ; No --> Use default
  554.     MOV    AX,RS232_BASE+2     ; Yes --> Use provided info
  555.     JMP    SHORT INST2        ; CONTINUE
  556.  
  557. INST3E8:MOV AX,3E8H            ; Standard COM3 location
  558.     CMP    RS232_BASE+4,0000H    ; We have information?
  559.      JE    INST2            ; No --> Use default
  560.     MOV    AX,RS232_BASE+4     ; Yes --> Use provided info
  561.     JMP    SHORT INST2        ; CONTINUE
  562.  
  563. INST2E8:MOV AX,2E8H            ; Standard COM4 location
  564.     CMP    RS232_BASE+6,0000H    ; We have information?
  565.      JE    INST2            ; No --> Use default
  566.     MOV    AX,RS232_BASE+6     ; Yes --> Use provided info
  567.     ; Fall into INST2
  568.  
  569.  
  570. ; Now we have an IO address for the COMx that we want to use.  If it is
  571. ; anywhere in RS232_Base, we know that it has been check and is OK to use.
  572. ; So, even if my 2E8 (COM4) appears in 40:6 (normally for COM3), I can use
  573. ; it.
  574.  
  575. INST2:    CMP    AX,RS232_BASE        ; INSTALLED?
  576.      JE    INST2A            ; JUMP IF SO
  577.     CMP    AX,RS232_BASE+2     ; INSTALLED?
  578.      JE    INST2A            ; JUMP IF SO
  579.     CMP    AX,RS232_BASE+4     ; INSTALLED?
  580.      JE    INST2A            ; JUMP IF SO
  581.     CMP    AX,RS232_BASE+6     ; INSTALLED?
  582.      JNE    INST666         ; JUMP IF NOT
  583.     ; Fall into INST2A
  584.  
  585. INST2A: MOV    BX,DATREG        ; OFFSET OF TABLE OF PORTS
  586.     MOV    CX,7            ; LOOP SIX TIMES
  587. INST3:    MOV    WORD PTR [SI][BX],AX    ; SET PORT ADDRESS
  588.     INC    AX            ; NEXT PORT
  589.     ADD    BX,2            ; NEXT WORD ADDRESS
  590.      LOOP    INST3            ; RS232 BASE LOOP
  591.     MOV DX,FCR[SI]            ; Get FIFO Control Register
  592.     MOV AL,FIFO_INIT
  593.     OUT DX,AL            ; Try to initialize the FIFO
  594.     MOV DX,IIR[SI]            ; Get interrupt ID register
  595.     IN AL,DX            ; See how the UART responded
  596.     AND AL,FIFO_ENABLED        ; Keep only these bits
  597.     MOV CX,1            ; Assume chunk size of 1 for 8250 case
  598.     CMP AL,FIFO_ENABLED        ; See if 16550A
  599.      JNE INST4            ; Jump if not
  600.     MOV CX,FIFO_LEN
  601. INST4:    MOV UART_SILO_LEN[SI],CL    ; Save chunk size for XMIT side only
  602.     MOV AL,FIFO_CLEAR
  603.     OUT DX,AL
  604.  
  605.     MOV    AH,25H            ; SET INTERRUPT VECTOR CONTENTS
  606.     MOV    AL,INT_COM[SI]        ; INTERRUPT NUMBER
  607.     MOV    DX,INT_HNDLR[SI]    ; OUR INTERRUPT HANDLER [WWP]
  608.     PUSH    DS            ; SAVE DATA SEGMENT
  609.     PUSH    CS            ; COPY CS
  610.     POP    DS            ; TO DS
  611.     INT    DOS            ; DOS FUNCTION
  612.     POP    DS            ; RECOVER DATA SEGMENT
  613.  
  614. ; PORT INSTALLED
  615. INST9:    MOV AX,1
  616.     JMP SHORT INSTX
  617.  
  618. ; PORT NOT INSTALLED
  619. INST666:MOV AX,0
  620.     ;Fall into INSTX
  621.  
  622. ; Common exit
  623. INSTX:    MOV INSTALLED[SI],AL        ; Indicate whether installed or not
  624.     POP ES
  625.     POP DI
  626.     POP SI
  627.     POPF                ; Restore caller's interrupt state
  628.     mov sp,bp
  629.     pop bp
  630.     RET
  631. _install_com ENDP
  632.     PAGE;
  633. ;
  634. ; void far restore_com(void)
  635. ;    Restore original interrupt vector and release storage
  636. ;
  637. _restore_com PROC FAR
  638.     push bp
  639.     mov bp,sp
  640.     PUSHF
  641.     PUSH SI
  642.     PUSH ES
  643.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  644.     CLI
  645.     MOV    INSTALLED[SI],0     ; PORT IS NO LONGER INSTALLED
  646.     MOV    AH,25H            ; SET INTERRUPT VECTOR FUNCTION
  647.     MOV    AL,INT_COM[SI]        ; INTERRUPT NUMBER
  648.     MOV    DX,OLD_COM_OFF[SI]    ; OLD OFFSET TO DX
  649.     MOV    BX,OLD_COM_SEG[SI]    ; OLD SEG
  650.     PUSH    DS            ; SAVE DS
  651.     MOV    DS,BX            ; TO DS
  652.     INT    DOS            ; DOS FUNCTION
  653.     POP DS                ; Recover our data segment
  654.  
  655.     MOV AX,WORD PTR TBuff+2[SI]    ; Transmit buffer paragraph
  656.     MOV ES,AX            ; Honest.  That's where the arg goes.
  657.     MOV AX,4900H            ; Release memory
  658.     INT DOS
  659.      ; Ignore error
  660.     MOV AX,WORD PTR RBuff+2[SI]    ; Receive buffer paragraph
  661.     MOV ES,AX
  662.     MOV AX,4900H
  663.     INT DOS
  664.      ; Ignore error
  665.     POP ES
  666.     POP SI
  667.     POPF
  668.     mov sp,bp
  669.     pop bp
  670.     RET
  671. _restore_com ENDP
  672.     PAGE;
  673. ;
  674. ; void far open_com(int Baud, char Conn, char Parity, char Stops, char Flow);
  675. ;
  676. ; CLEAR BUFFERS
  677. ; RE-INITIALIZE THE UART
  678. ; ENABLE INTERRUPTS ON THE 8259 INTERRUPT CONTROL CHIP
  679. ;
  680. ; [bp+6] = BAUD RATE
  681. ; [bp+8] = CONNECTION: M(ODEM), D(IRECT)
  682. ; [bp+10] = PARITY:    N(ONE), O(DD), E(VEN), S(PACE), M(ARK)
  683. ; [bp+12] = STOP BITS:    1, 2
  684. ; [bp+14] = XON/XOFF:    E(NABLED), D(ISABLED)
  685. ;
  686. _open_com PROC FAR
  687.     push bp
  688.     mov bp,sp
  689.     PUSHF
  690.     PUSH SI
  691.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  692.     CLI                ; INTERRUPTS OFF
  693.     TEST INSTALLED[SI],1        ; Port installed?
  694.      JNZ OPEN1            ; Yes --> Proceed
  695.      JMP OPENX            ; No  --> Get out
  696.  
  697. OPEN1:    mov ax,[bp+6]
  698.     MOV    BAUD_RATE[SI],AX    ; SET
  699.     mov bh,[bp+8]
  700.     MOV    CONNECTION[SI],BH    ; ARGS
  701.     mov bl,[bp+10]
  702.     MOV    PARITY[SI],BL        ; IN
  703.     mov ch,[bp+12]
  704.     MOV    STOP_BITS[SI],CH    ; MEMORY
  705.     mov cl,[bp+14]
  706.     MOV    XON_XOFF[SI],CL
  707.  
  708. ; RESET FLOW CONTROL
  709.     MOV    HOST_OFF[SI],0        ; HOST FLOWING
  710.     MOV    PC_OFF[SI],0        ; PC FLOWING
  711.     MOV URGENT_SEND[SI],0        ; No (high priority) flow ctl
  712.     MOV SEND_OK[SI],0        ; DTR&CTS are not on yet
  713.  
  714. ; RESET BUFFER COUNTS AND POINTERS
  715.     MOV    START_TDATA[SI],0
  716.     MOV    END_TDATA[SI],0
  717.     MOV    START_RDATA[SI],0
  718.     MOV    END_RDATA[SI],0
  719.     MOV    SIZE_TDATA[SI],0
  720.     MOV    SIZE_RDATA[SI],0
  721.  
  722. ;
  723. ; RESET THE UART
  724.     MOV DX,MCR[SI]            ; Modem Control Register
  725.     IN AL,DX            ; Get current settings
  726.     AND AL,0FEH            ; Clr RTS, OUT1, OUT2 & LOOPBACK, but
  727.     OUT DX,AL            ; Not DTR (No hangup during autobaud)
  728.     MOV DX,MSR[SI]            ; Modem Status Register
  729.     IN AL,DX            ; Get current DSR and CTS states.
  730.     AND AL,30H            ; Init PREVIOUS STATE FLOPS to current
  731.     OUT DX,AL            ;  state and clear Loopback, etc.
  732.     IN AL,DX            ; Re-read to get delta bits & clr int
  733.     AND AL,30H            ; Leave the two critical bits
  734.     CMP AL,30H            ; Both on?
  735.      JNE OPEN2            ; No.  Leave SEND_OK zero.
  736.     MOV SEND_OK[SI],1        ; Allow TXI to send out data
  737. OPEN2:    MOV DX,FCR[SI]            ; I/O Address of FIFO control register
  738.     MOV AL,FIFO_CLEAR        ; Disable FIFOs
  739.     OUT DX,AL            ; Non-16550A chips will ignore this
  740.     MOV    DX,LSR[SI]        ; RESET LINE STATUS CONDITION
  741.     IN    AL,DX
  742.     MOV    DX,DATREG[SI]        ; RESET RECEIVE DATA CONDITION
  743.     IN    AL,DX
  744.     MOV    DX,MSR[SI]        ; RESET MODEM DELTAS AND CONDITIONS
  745.     IN    AL,DX
  746.  
  747.     CALL Set_Baud            ; Set the baud rate from arg
  748.     PAGE;
  749. ; SET PARITY AND NUMBER OF STOP BITS
  750.     MOV    AL,03H            ; Default: NO PARITY + 8 bits data
  751.  
  752.     CMP    PARITY[SI],'O'          ; ODD PARITY REQUESTED?
  753.      JNE    P1            ; JUMP IF NOT
  754.     MOV    AL,0AH            ; SELECT ODD PARITY + 7 bits data
  755.     JMP    SHORT P4        ; CONTINUE
  756. ;
  757. P1:    CMP    PARITY[SI],'E'          ; EVEN PARITY REQUESTED?
  758.      JNE    P2            ; JUMP IF NOT
  759.     MOV    AL,1AH            ; SELECT EVEN PARITY + 7 bits data
  760.     JMP    SHORT P4        ; CONTINUE
  761. ;
  762. P2:    CMP    PARITY[SI],'M'          ; MARK PARITY REQUESTED?
  763.      JNE    P3            ; JUMP IF NOT
  764.     MOV    AL,2AH            ; SELECT MARK PARITY + 7 bits data
  765.     JMP SHORT P4
  766.  
  767. P3:    CMP PARITY[SI],'S'              ; SPACE parity requested?
  768.      JNE P4             ; No.  Must be 'N' (NONE)
  769.     MOV AL,3AH            ; Select SPACE PARITY + 7 bits data
  770.  
  771. P4:    TEST    STOP_BITS[SI],2     ; 2 STOP BITS REQUESTED?
  772.      JZ    STOP1            ; NO
  773.     OR    AL,4            ; YES
  774. STOP1:    MOV    DX,LCR[SI]        ; LINE CONTROL REGISTER
  775.     OUT    DX,AL            ; SET UART PARITY MODE AND DLAB=0
  776.  
  777. ; Initialize the FIFOs
  778.     MOV    DX,FCR[SI]        ; I/O Address of FIFO control register
  779.     MOV    AL,FIFO_INIT        ; Clear FIFOs, set size, enable FIFOs
  780.     OUT    DX,AL            ; Non-16550A chips will ignore this
  781.  
  782. ; ENABLE INTERRUPTS ON 8259 AND UART
  783.     IN    AL,INTA01        ; SET ENABLE BIT ON 8259
  784.     AND    AL,NIRQ[SI]
  785.     OUT    INTA01,AL
  786.     MOV DX,IER[SI]            ; Interrupt enable register
  787.     MOV AL,0DH            ; Line & Modem status, recv [GT]
  788.     OUT DX,AL            ; Enable those interrupts
  789.  
  790. OPENX:    POP SI
  791.     POPF                ; Restore interrupt state
  792.     mov sp,bp
  793.     pop bp
  794.     RET                ; DONE
  795. _open_com ENDP
  796.     PAGE;
  797. ;
  798. ; void far ioctl_com(int Flags, int Arg1, ...)
  799. ;    Flags have bits saying what to do or change (IGNORED TODAY)
  800. ;    Arg1, ...  are the new values
  801. ;
  802. _ioctl_com PROC FAR
  803.     PUSH BP
  804.     MOV BP,SP
  805.     PUSHF                ; Save interrupt context
  806.     PUSH SI
  807.     MOV SI,CURRENT_AREA        ; Pointer to COMi private area
  808.     CLI                ; Prevent surprises
  809.     TEST INSTALLED[SI],1
  810.      JE IOCTLX            ; No good.  Just return.
  811.     MOV AX,[BP+6]            ; Flags
  812.     ; Check bits here...
  813.     MOV AX,[BP+8]            ; Line speed
  814.     MOV BAUD_RATE[SI],AX        ; Save in parameter block
  815.     CALL Set_Baud            ; Set the baud rate in UART
  816. IOCTLX: POP SI
  817.     POPF                ; Restore interrupt state
  818.     MOV SP,BP
  819.     POP BP
  820.     RET
  821. _ioctl_com    ENDP
  822.     PAGE;
  823. ; ioctl-called routines (internal) ...
  824.  
  825. ; SI:    COMi private block
  826. ;    CALL Set_Baud
  827. ; Returns: (nothing)
  828. ; Clobber: AX, BX, DX
  829.  
  830. Set_Baud PROC NEAR
  831.     MOV AX,50
  832.     MUL DIV50            ; Could be different on a PCJr!
  833.     DIV BAUD_RATE[SI]        ; Get right number for the UART
  834.     MOV BX,AX            ; Save it
  835.     MOV DX,LCR[SI]            ; Line Control Register
  836.     IN AL,DX            ; Get current size, stops, parity,...
  837.     PUSH AX
  838.     OR AL,80H            ; DLAB bit
  839.     OUT DX,AL            ; Talk to the baud rate regs now
  840.     MOV DX,WORD PTR DLL[SI]     ; Least significant byte
  841.     MOV AL,BL            ; New value
  842.     OUT DX,AL            ; To UART
  843.     MOV DX,WORD PTR DLH[SI]     ; Most signifiant byte
  844.     MOV AL,BH            ; New value
  845.     OUT DX,AL
  846.     MOV DX,LCR[SI]            ; Line Control Register
  847.     POP AX
  848.     OUT DX,AL            ; Turn off DLAB, keep saved settings
  849.     RET
  850. Set_Baud ENDP
  851.     PAGE;
  852. ;
  853. ; void far close_com(void)
  854. ;    Turn off interrupts from the COM port
  855. ;
  856. _close_com PROC FAR
  857.     push bp
  858.     mov bp,sp
  859.     PUSHF
  860.     PUSH SI
  861.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  862.     TEST    INSTALLED[SI],1     ; PORT INSTALLED?
  863.      JZ    CCX            ; ABORT IF NOT
  864.  
  865. ; TURN OFF UART and clear FIFOs in NS16550A
  866.     CLI
  867.     MOV DX,IER[SI]
  868.     MOV AL,0
  869.     OUT DX,AL            ; No interrupts right now, please
  870.     MOV DX,FCR[SI]            ; FIFO Control Register
  871.     MOV AL,FIFO_CLEAR        ; Disable FIFOs
  872.     OUT DX,AL
  873.     MOV DX,MCR[SI]            ; Modem control register
  874.     XOR AL,AL            ; OUT2 is IRQ enable on some machines,
  875.     OUT DX,AL            ; So, clear RTS, OUT1, OUT2, LOOPBACK
  876.  
  877. ; TURN OFF 8259
  878.     MOV    DX,INTA01
  879.     IN    AL,DX
  880.     OR    AL,IRQ[SI]
  881.     JMP    $+2            ; DELAY FOR AT
  882.     JMP    $+2            ; DELAY FOR AT
  883.     JMP    $+2            ; DELAY FOR AT
  884.     OUT    DX,AL
  885.  
  886. CCX:    POP SI
  887.     POPF                ; Restore interrupt state
  888.     mov sp,bp
  889.     pop bp
  890.     RET
  891. _close_com ENDP
  892.     PAGE;
  893. ;
  894. ; void far dtr_off(void)
  895. ;    Tells modem we are done.  Remote end should hang up also.
  896. ;
  897. _dtr_off PROC FAR
  898.     push bp
  899.     mov bp,sp
  900.     PUSH SI
  901.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  902.     TEST    INSTALLED[SI],1     ; PORT INSTALLED?
  903.      JZ    DFX            ; ABORT IF NOT
  904.  
  905.     MOV DX,MCR[SI]            ; Modem Control Register
  906.     IN AL,DX            ; Get current state
  907.     PUSH AX             ; Save MCR
  908.     MOV AL,08H            ; DTR off, RTS off, OUT2 on
  909.     OUT DX,AL
  910.     POP AX                ; Get previous state
  911.     AND AL,1            ; Just look at the DTR bit
  912.      JE DFX             ; Not on.  Don't clr.  Don't wait.
  913.     MOV AX,50            ; 50/100 of second
  914. IFNDEF UUPC
  915.     CALL WaitN            ; V.24 says it must be low >1/2 sec
  916. ENDIF
  917. DFX:    POP SI
  918.     mov sp,bp
  919.     pop bp
  920.     RET
  921. _dtr_off    ENDP
  922.     PAGE;
  923. ;
  924. ; void far dtr_on(void)     Tell modem we can take traffic
  925. ;
  926. _dtr_on PROC FAR
  927.     push bp
  928.     mov bp,sp
  929.     PUSH SI
  930.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  931.     TEST    INSTALLED[SI],1     ; PORT INSTALLED?
  932.      JZ DTRONF            ; Suppress output if not
  933.  
  934. ; Tell modem we are ready and want to send with line idle
  935.  
  936.     MOV DX,MCR[SI]            ; Modem Control Register
  937.     MOV AL,00001011B        ; OUT 2, RTS, DTR
  938.     OUT DX,AL
  939.     CMP CONNECTION[SI],'D'          ; Direct connection (no DSR,CTS)?
  940.      JNE DTRON0            ; Go wait for DSR, CTS
  941.     MOV SEND_OK[SI],1        ; Set output enable flag
  942.     JMP SHORT DTRONS        ; Give success return
  943.  
  944. ; Wait for awhile to give the modem time to respond
  945.  
  946. DTRON0: MOV AH,2CH            ; Get time (H:M:S:H to CH:CL:DH:DL)
  947.     INT 21H
  948.     MOV BX,DX            ; Save seconds&hundreths
  949.     ADD BH,06            ; Allow a few seconds
  950.     CMP BH,60            ; Wrap around check
  951.      JL DTRON1            ; No wrap
  952.     SUB BH,60
  953. DTRON1: CMP SEND_OK[SI],1        ; Did the modem come up?
  954.      JE DTRONS            ; Yes.    Both DSR and CTS are true.
  955.     INT 21H             ; Get the time again
  956.     CMP DX,BX            ; Current time is passed the deadline?
  957.      JB DTRON1            ; No, keep checking 'til time runs out
  958.  
  959.     ; Modem failed to come up.  Bump counts that tell why.
  960.     MOV    DX,MSR[SI]        ; MODEM STATUS REGISTER
  961.     IN    AL,DX            ; GET MODEM STATUS
  962.     TEST    AL,20H            ; DATA SET READY?
  963.      JNZ DTRON6            ; Yup.
  964.     INC    WORD PTR EDSR[SI]    ; BUMP ERROR COUNT
  965. DTRON6: TEST    AL,10H            ; Clear To Send?
  966.      JNZ DTRONF            ; That's OK.
  967.     INC    WORD PTR ECTS[SI]    ; BUMP ERROR COUNT - WE TIMED OUT
  968.     ; Fall into DTRONF
  969.     PAGE;
  970. ; Failure return
  971.  
  972. DTRONF: MOV SEND_OK[SI],1        ; Make believe DSR & CTS are up!!!
  973.     MOV CONNECTION[SI],'D'          ; Switch to DIR connection (MSTATINT)
  974.     JMP SHORT DTRONX
  975.  
  976.  
  977. ; Successful return
  978.  
  979. DTRONS: ; SEND_OK is on.  Setting it again could confuse interrupt level
  980.     ; Fall into DTRONX
  981.  
  982. DTRONX: MOV AX,200H            ; 2 Seconds
  983. IFNDEF UUPC
  984.     CALL WaitN            ; V.24 says 2 sec hi before data
  985. ENDIF
  986.     POP SI
  987.     mov sp,bp
  988.     pop bp
  989.     RET
  990. _dtr_on ENDP
  991.     PAGE;
  992. ;
  993. ; Wait for specified time using the 18.2 ticks/second clock
  994. ;
  995. ; Call:     AX has seconds,hundreths
  996. ;        CALL WaitN
  997. ; Return:    At least the requested time has passed
  998. ;
  999.  
  1000. WaitN    PROC NEAR
  1001.     PUSH BP
  1002.     MOV BP,SP
  1003.     PUSH AX
  1004.     PUSH BX
  1005.     PUSH CX
  1006.     PUSH DX
  1007.     PUSH AX             ; Save a copy of the arg
  1008.     MOV AH,2CH            ; Get time (H:M:S:H to CH:CL:DH:DL)
  1009.     INT DOS
  1010.     POP BX                ; Recover S:H arg
  1011.     ADD BX,DX            ; Determine deadline
  1012.     CMP BL,100            ; Wrap around?
  1013.      JL WaitN1            ; No
  1014.     SUB BL,100            ; Yes.    Subtract 100 hundreths
  1015.     INC BH                ; And add a second
  1016. WaitN1: CMP BH,60            ; Wrap around check
  1017.      JL WaitN2            ; No wrap
  1018.     SUB BH,60            ; Forget about Days and Hours
  1019. WaitN2: INT DOS             ; Get the time again
  1020.     CMP DX,BX            ; Is current time after the deadline?
  1021.      JB WaitN2            ; No, keep checking 'til time runs out
  1022.     POP DX
  1023.     POP CX
  1024.     POP BX
  1025.     POP CX
  1026.     MOV SP,BP
  1027.     POP BP
  1028.     RET
  1029. WaitN    ENDP
  1030.     PAGE;
  1031. ;
  1032. ; unsigned long r_count(void)
  1033. ;    Value is really two uints:  Buffer size in high half, count in low.
  1034. ;    Count returned is <= number of chars waiting to be read.
  1035. ;        (More may come in after you asked.)
  1036. ;
  1037. _r_count PROC FAR
  1038.     push bp
  1039.     mov bp,sp
  1040.     PUSH SI
  1041.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  1042.     XOR AX,AX            ; Say nothing available if not inst'd
  1043.     MOV DX,R_SIZE            ; Size of entire receive buffer
  1044.     TEST    INSTALLED[SI],1     ; PORT INSTALLED?
  1045.      JZ    RCX            ; ABORT IF NOT
  1046.     MOV    AX,SIZE_RDATA[SI]    ; GET NUMBER OF BYTES USED
  1047. RCX:    POP SI
  1048.     mov sp,bp
  1049.     pop bp
  1050.     RET
  1051. _r_count ENDP
  1052.     PAGE;
  1053. ;
  1054. ; char far receive_com(void)
  1055. ;    Returns AX: -1 if port not installed or no characters available
  1056. ;        or AX: the next character with parity stipped if not in P mode
  1057. ;
  1058. _receive_com PROC FAR
  1059.     push bp
  1060.     mov bp,sp
  1061.     PUSHF                ; Save interrupt state
  1062.     PUSH SI
  1063.     PUSH ES
  1064.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  1065.     mov    ax,-1            ; -1 if bad call
  1066.     TEST    INSTALLED[SI],1     ; PORT INSTALLED?
  1067.      JZ    RECVX            ; ABORT IF NOT
  1068.     CLI
  1069.     CMP    SIZE_RDATA[SI],0    ; ANY CHARACTERS?
  1070.      JE RECVX            ; Return -1 in AX
  1071.  
  1072.     mov ah,0            ; good call
  1073.     LES    BX,RBuff[SI]        ; Location of receive buffer
  1074.     ADD    BX,START_RDATA[SI]    ; GET POINTER TO OLDEST CHAR
  1075.     MOV AL,ES:[BX]            ; Get character from buffer
  1076.     CMP    PARITY[SI],'N'          ; ARE WE RUNNING WITH NO PARITY? LBA
  1077.      JE    RECV1            ; IF SO, DON'T STRIP HIGH BIT    LBA
  1078.     AND    AL,7FH            ; STRIP PARITY BIT
  1079. RECV1:    MOV BX,START_RDATA[SI]        ; Get the start index again
  1080.     INC    BX            ; BUMP START_RDATA
  1081.     AND BX,R_SIZE-1         ; Ring the pointer
  1082.     MOV    START_RDATA[SI],BX    ; SAVE THE NEW START_RDATA VALUE
  1083.     DEC    SIZE_RDATA[SI]        ; ONE LESS CHARACTER
  1084.     CMP    XON_XOFF[SI],'E'        ; FLOW CONTROL ENABLED?
  1085.      JNE    RECVX            ; DO NOTHING IF DISABLED
  1086.     CMP    HOST_OFF[SI],1        ; HOST TURNED OFF?
  1087.      JNE    RECVX            ; JUMP IF NOT
  1088.     CMP    SIZE_RDATA[SI],R_SIZE/16; RECEIVE BUFFER NEARLY EMPTY?
  1089.      JGE    RECVX            ; DONE IF NOT
  1090.     MOV    HOST_OFF[SI],0        ; TURN ON HOST IF SO
  1091.  
  1092.     PUSH    AX            ; SAVE RECEIVED CHAR
  1093.     MOV    AL,CONTROL_Q        ; TELL HIM TO TALK
  1094. RECV3:    CLI                ; TURN OFF INTERRUPTS
  1095.     CMP URGENT_SEND[SI],1        ; Previous send still in progress?
  1096.      JNE RECV4            ; No.  There is space now.
  1097.     STI                ; Yes.    Wait for interrupt to take it.
  1098.     JMP SHORT RECV3         ; Loop 'til it's gone
  1099. RECV4:    CALL    SENDII            ; SEND IMMEDIATELY INTERNAL
  1100.     POP    AX            ; RESTORE RECEIVED CHAR
  1101.  
  1102. RECVX:    POP ES
  1103.     POP SI
  1104.     POPF                ; Restore interrupt state
  1105.     mov sp,bp
  1106.     pop bp
  1107.     RET
  1108. _receive_com ENDP
  1109.     PAGE;
  1110. ;
  1111. ; unsigned long s_count(void)
  1112. ;    Value is really two uints: Buffer size in high half (returned in DX).
  1113. ;                Free space count in low (returned in AX).
  1114. ;    Count returned is <= number of chars which can be sent without blocking.
  1115. ;        (More may become available after you asked.)
  1116. ;
  1117. ; N.B. The free space might be negative (-1) if the buffer was full and then
  1118. ; the program called SENDI or RXI required sending a control-S to squelch
  1119. ; the remote sender.  Return 0 in this case.
  1120. ;
  1121. _s_count PROC FAR
  1122.     push bp
  1123.     mov bp,sp
  1124.     PUSH SI
  1125.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  1126.     MOV    AX,0            ; NO SPACE LEFT IF NOT INSTALLED
  1127.     mov dx,S_SIZE-1         ; Leave 1 byte for a SENDII call
  1128.     TEST    INSTALLED[SI],1     ; PORT INSTALLED?
  1129.      JZ    SCX            ; ABORT IF NOT
  1130.     MOV AX,S_SIZE-1         ; Size, keeping one aside for SENDII
  1131.     SUB AX,SIZE_TDATA[SI]        ; Minus number in use right now
  1132.      JGE SCX            ; Avoid returning negative number
  1133.     XOR AX,AX            ; Return 0
  1134. SCX:    POP SI
  1135.     mov sp,bp
  1136.     pop bp
  1137.     RET
  1138. _s_count ENDP
  1139.     PAGE;
  1140. ;
  1141. ; void far send_com(char)
  1142. ;    Send a character to the selected port
  1143. ;
  1144. _send_com PROC FAR
  1145.     push bp
  1146.     mov bp,sp
  1147.     PUSHF                ; Save interrupt state
  1148.     PUSH SI
  1149.     PUSH ES
  1150.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  1151.     TEST    INSTALLED[SI],1     ; PORT INSTALLED?
  1152.      JZ    SENDX            ; ABORT IF NOT
  1153.  
  1154. SEND1:    CMP    SIZE_TDATA[SI],S_SIZE-1 ; BUFFER FULL? (Leave room for SENDII)
  1155.      JGE SEND1            ; Wait for interrupts to empty buffer
  1156.     CLI
  1157.     LES BX,TBUFF[SI]        ; Pointer to buffer
  1158.     ADD BX,END_TDATA[SI]        ; ES:BX points to free space
  1159.     MOV AL,[BP+6]            ; Character to send
  1160.     MOV ES:[BX],AL            ; Move character to buffer
  1161.     MOV BX,END_TDATA[SI]        ; Get index of end
  1162.     INC    BX            ; INCREMENT END_TDATA
  1163.     AND BX,S_SIZE-1         ; Ring the pointer
  1164.     MOV    END_TDATA[SI],BX    ; SAVE NEW END_TDATA
  1165.     INC    SIZE_TDATA[SI]        ; ONE MORE CHARACTER IN X-MIT BUFFER
  1166.  
  1167.     TEST PC_OFF[SI],1        ; Were we stopped by a ^S from host?
  1168.      JNZ SENDX            ; Yes.    Don't enable interrupts yet.
  1169.     CALL CHROUT            ; Put a character out to the UART
  1170. SENDX:    POP ES
  1171.     POP SI
  1172.     POPF                ; Restore interrupt state
  1173.     mov sp,bp
  1174.     pop bp
  1175.     RET
  1176. _send_com ENDP
  1177.     PAGE;
  1178. ;
  1179. ; void far sendi_com(char)
  1180. ;    Send a character immediately by placing it at the head of the queue
  1181. ;
  1182. _sendi_com PROC FAR
  1183.     push bp
  1184.     mov bp,sp
  1185.     PUSHF                ; Save interrupt state
  1186.     PUSH SI
  1187.     mov al,[bp+6]
  1188.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  1189.     TEST    INSTALLED[SI],1     ; PORT INSTALLED?
  1190.      JZ SENDIX            ; Return if not
  1191.  
  1192. SENDI3: CLI                ; TURN OFF INTERRUPTS
  1193.     CMP URGENT_SEND[SI],1        ; Previous send still in progress?
  1194.      JNE SENDI4            ; No.  There is space now.
  1195.     STI                ; Yes.    Wait for interrupt to take it.
  1196.     JMP SHORT SENDI3        ; Loop 'til it's gone
  1197.  
  1198. SENDI4: CALL    SENDII            ; CALL INTERNAL SEND IMMEDIATE
  1199.  
  1200. SENDIX: POP SI
  1201.     POPF                ; Restore interrupt state
  1202.     mov sp,bp
  1203.     pop bp
  1204.     RET
  1205. _sendi_com ENDP
  1206.     PAGE;
  1207. ; SENDII(AL, SI)  [internal routine]
  1208. ;    Put char at head of output queue so it will go out next
  1209. ;    Called from process level and (receive) interrupt level
  1210. ;    DEPENDS ON CALLER TO KEEP INTERRUPTS CLEARED AND SET SI
  1211. ;
  1212. SENDII    PROC NEAR
  1213.     PUSH BX
  1214.     PUSH DX
  1215.     PUSH ES
  1216.     LES BX,TBuff[SI]        ; Location of transmit buffer
  1217.     CMP    SIZE_TDATA[SI],S_SIZE    ; BUFFER FULL?
  1218.      JB    SENDII2         ; JUMP IF NOT
  1219.     INC    WORD PTR EOVFLOW[SI]    ; BUMP ERROR COUNT (Can this happen?)
  1220.     ADD BX,START_TDATA[SI]        ; ES:BX point to 1st chr in buffer
  1221.     MOV ES:[BX],AL            ; Overwrite 1st character
  1222.     JMP SHORT SENDII4
  1223.  
  1224. SENDII2:MOV DX,START_TDATA[SI]        ; DX is index of 1st char
  1225.     DEC DX                ; Back it up
  1226.     AND DX,S_SIZE-1         ; Ring it
  1227.     MOV START_TDATA[SI],DX        ; Save new value
  1228.     ADD BX,DX            ; Address within buffer
  1229.     MOV ES:[BX],AL            ; Move character to buffer
  1230.     INC    SIZE_TDATA[SI]        ; ONE MORE CHARACTER IN X-MIT BUFFER
  1231.     MOV URGENT_SEND[SI],1        ; Flag high priority message
  1232.     ; No check for PC_OFF here.  Flow control ALWAYS gets sent!
  1233. SENDII4:CALL CHROUT            ; Output a chr if possible
  1234. SENDIIX:POP ES
  1235.     POP DX
  1236.     POP BX
  1237.     RET
  1238. SENDII    ENDP
  1239.  
  1240.  
  1241.  
  1242. ; CHROUT()    Process level routine to remove a chr from the buffer,
  1243. ;        give it to the UART and adjust the pointer and count.
  1244. ;        If interrupts are disabled at entry, nothing is done.
  1245. ;        If a character is successfully output, Tx ints are enabled.
  1246. ;    Requires: SI pointing at the appropriate data area
  1247. ;    Clobbers: AX, BX, DX, ES
  1248. ;    Must preserve: CX in case there is a count there
  1249.  
  1250. CHROUT    PROC NEAR
  1251.     MOV DX,IER[SI]            ; Interrupt Enable Register
  1252.     IN AL,DX
  1253.     TEST AL,2            ; Tx interrupts enabled?
  1254.      JNZ CHROUX            ; Jump if not
  1255.     CMP SEND_OK[SI],1        ; See if Data Set Ready & CTS are on
  1256.      JNE CHROUX            ; No. Still can't enable TX ints
  1257.     CALL TX_CHR            ; Actually transmit the chr
  1258.     MOV DX,IER[SI]            ; Interrupt Enable Register
  1259.     MOV AL,0FH            ; Rx, Tx, Line & Modem enable bits
  1260.     OUT DX,AL            ; Enable those interrupts
  1261. CHROUX: RET
  1262. CHROUT    ENDP
  1263.     PAGE;
  1264.  
  1265. IFNDEF UUPC
  1266. ;
  1267. ; void far send_local(char);
  1268. ;    Simulate a loopback by placing characters sent in recv buffer
  1269. ;
  1270. _send_local PROC FAR
  1271.     push bp
  1272.     mov bp,sp
  1273.     PUSHF
  1274.     PUSH SI
  1275.     PUSH ES
  1276.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  1277.     TEST    INSTALLED[SI],1     ; PORT INSTALLED?
  1278.      JZ    SLX            ; ABORT IF NOT
  1279.  
  1280.     CLI                ; INTERRUPTS OFF
  1281.     CMP    SIZE_RDATA[SI],R_SIZE    ; SEE IF ANY ROOM
  1282.      JB SL3             ; SKIP IF ROOM
  1283.     INC    WORD PTR EOVFLOW[SI]    ; BUMP OVERFLOW COUNT
  1284.     JMP SHORT SLX            ; PUNT
  1285.  
  1286. SL3:    LES BX,RBuff[SI]        ; Receive buffer location
  1287.     ADD BX,END_RDATA[SI]        ; ES:BX POINTS TO FREE SPACE
  1288.     MOV AL,[BP+6]            ; Get the byte to send
  1289.     MOV ES:[BX],AL            ; Put into buffer
  1290.     MOV BX,END_RDATA[SI]        ; Get the end pointer
  1291.     INC    BX            ; INCREMENT END_RDATA POINTER
  1292.     AND BX,R_SIZE-1         ; Ring the pointer
  1293.     MOV    END_RDATA[SI],BX    ; SAVE VALUE
  1294.     INC    SIZE_RDATA[SI]        ; GOT ONE MORE CHARACTER
  1295.  
  1296. SLX:    POP ES
  1297.     POP SI
  1298.     POPF                ; Restore interrupt state
  1299.     mov sp,bp
  1300.     pop bp
  1301.     RET                ; DONE
  1302. _send_local    ENDP
  1303. ENDIF
  1304.     PAGE;
  1305. ;
  1306. ; void far break_com(void)    Send a BREAK out to alert the remote end
  1307. ;
  1308. _break_com PROC FAR
  1309.     push bp
  1310.     mov bp,sp
  1311.     PUSH SI
  1312.  
  1313.     MOV    SI,CURRENT_AREA     ; SI POINTS TO DATA AREA
  1314.     TEST    INSTALLED[SI],1     ; PORT INSTALLED?
  1315.      JZ    BREAKX            ; ABORT IF NOT
  1316.  
  1317.     MOV    DX,LCR[SI]        ; LINE CONTROL REGISTER
  1318.     IN    AL,DX            ; GET CURRENT SETTING
  1319.     OR    AL,40H            ; TURN ON BREAK BIT
  1320.     OUT    DX,AL            ; SET IT ON THE UART
  1321.     MOV AX,25            ; 25/100 of a second
  1322.     CALL WaitN
  1323.     MOV    DX,LCR[SI]        ; LINE CONTROL REGISTER
  1324.     IN    AL,DX            ; GET CURRENT SETTING
  1325.     AND    AL,0BFH         ; TURN OFF BREAK BIT
  1326.     OUT    DX,AL            ; RESTORE LINE CONTROL REGISTER
  1327. BREAKX: POP SI
  1328.     mov sp,bp
  1329.     pop bp
  1330.     RET
  1331. _break_com ENDP
  1332.     PAGE;
  1333. ;
  1334. ; ERROR_STRUCT far *com_errors(void)
  1335. ;    Returns a pointer to the table of error counters
  1336. ;
  1337. _com_errors PROC FAR
  1338.     push bp
  1339.     mov bp,sp
  1340.     PUSH SI
  1341.     MOV SI,CURRENT_AREA        ; Point to block for selected port
  1342.     LEA AX,ERROR_BLOCK[SI]        ; Offset to error counters
  1343.     MOV DX,DS            ; Value is in DX:AX
  1344.     POP SI
  1345.     mov sp,bp
  1346.     pop bp
  1347.     RET
  1348. _com_errors ENDP
  1349.  
  1350.  
  1351.  
  1352.  
  1353.  
  1354.  
  1355. ;
  1356. ; char far modem_status(void)
  1357. ;    Returns the modem status register in AL
  1358. ;
  1359. ; Bits are:    0x80:    Carrier Detect
  1360. ;        0x40:    Ring Indicator
  1361. ;        0x20:    Data Set Ready
  1362. ;        0x10:    Clear To Send
  1363. ;        0x08:    Delta Carrier Detect    (CD changed)
  1364. ;        0x04:    Trailing edge of RI    (RI went OFF)
  1365. ;        0x02:    Delta DSR        (DSR changed)
  1366. ;        0x01:    Delta CTS        (CTS changed)
  1367.  
  1368. _modem_status PROC FAR
  1369.     push bp
  1370.     mov bp,sp
  1371.     PUSH SI
  1372.     MOV SI,CURRENT_AREA        ; Point to block for selected port
  1373.     MOV DX,MSR[SI]            ; IO Addr of Modem Status Register
  1374.     IN AL,DX            ; Get the live value
  1375.     XOR AH,AH            ; Flush unwanted bits
  1376.     POP SI
  1377.     mov sp,bp
  1378.     pop bp
  1379.     RET
  1380. _modem_status ENDP
  1381.     PAGE;
  1382. ;
  1383. ; INT_HNDLR1 - HANDLES INTERRUPTS GENERATED BY COM1:
  1384. ;
  1385. INT_HNDLR1 PROC FAR
  1386.     PUSH SI
  1387.     MOV    SI,OFFSET DGROUP:AREA1    ; DATA AREA FOR COM1:
  1388.     JMP    SHORT INT_COMMON    ; CONTINUE
  1389. ;
  1390. ; INT_HNDLR2 - HANDLES INTERRUPTS GENERATED BY COM2:
  1391. ;
  1392. INT_HNDLR2 PROC FAR
  1393.     PUSH SI
  1394.     MOV    SI,OFFSET DGROUP:AREA2    ; DATA AREA FOR COM2:
  1395.     JMP    SHORT INT_COMMON    ; CONTINUE
  1396. ;
  1397. ; INT_HNDLR3 - HANDLES INTERRUPTS GENERATED BY COM3:
  1398. ;
  1399. INT_HNDLR3 PROC FAR
  1400.     PUSH SI
  1401.     MOV    SI,OFFSET DGROUP:AREA3    ; DATA AREA FOR COM3:
  1402.     JMP    SHORT INT_COMMON    ; CONTINUE
  1403. ;
  1404. ; INT_HNDLR4 - HANDLES INTERRUPTS GENERATED BY COM4:
  1405. ;
  1406. INT_HNDLR4 PROC FAR
  1407.     PUSH SI
  1408.     MOV    SI,OFFSET DGROUP:AREA4    ; DATA AREA FOR COM4:
  1409.     ; Fall into INT_COMMON
  1410.     PAGE;
  1411. ;
  1412. ; BODY OF INTERRUPT HANDLER
  1413. ;
  1414. INT_COMMON: ; SI has been pushed and loaded
  1415.     PUSH AX
  1416.     PUSH BX
  1417.     PUSH CX
  1418.     PUSH DX
  1419.     PUSH DS
  1420.     PUSH ES
  1421.  
  1422.     MOV AX,DGROUP            ; Offsets are relative to DGROUP [WWP]
  1423.     MOV    DS,AX
  1424.  
  1425.  
  1426. ; FIND OUT WHERE INTERRUPT CAME FROM AND JUMP TO ROUTINE TO HANDLE IT
  1427. REPOLL: MOV DX,IIR[SI]            ; Interrupt Identification Register
  1428.     IN AL,DX
  1429.     TEST AL,1            ; Check the "no interrupt present" bit
  1430.      JNZ INT_END            ; ON means we are done
  1431.     MOV BL,AL            ; Put where we can index by it
  1432.     AND BX,000EH            ; Ignore FIFO_ENABLED bits, etc.
  1433.  
  1434.     JMP WORD PTR CS:INT_DISPATCH[BX]; Go to appropriate routine
  1435.  
  1436. INT_DISPATCH:
  1437.     DW MSI                ; 0: Modem status interrupt
  1438.     DW TXI                ; 2: Transmitter interrupt
  1439.     DW RXI                ; 4: Receiver interrupt
  1440.     DW LSI                ; 6: Line status interrupt
  1441.     DW REPOLL            ; 8: (Future use by UART makers)
  1442.     DW REPOLL            ; A: (Future use by UART makers)
  1443.     DW RXI                ; C: FIFO Timeout
  1444.     DW REPOLL            ; E: (Future use by UART makers)
  1445.  
  1446. INT_END: ; Now tell 8259 we handled that IRQ
  1447.  
  1448.     MOV DX,IER[SI]            ; Gordon Lee's cure for dropped ints
  1449.     IN AL,DX            ; Get enabled interrupts
  1450.     MOV AH,AL
  1451.     XOR AL,AL
  1452.     OUT DX,AL            ; Disable UART interrupts
  1453.     MOV AL,EOI[SI]            ; End of Interrupt. With input gone,
  1454.     OUT INTA00,AL            ; Give EOI to 8259 Interrupt ctlr
  1455.     MOV AL,AH            ; Get save interrupt enable bits
  1456.     OUT DX,AL            ; Restore them, maybe causing a
  1457.                     ; transition into the 8259!!!
  1458.     POP ES
  1459.     POP DS
  1460.     POP DX
  1461.     POP CX
  1462.     POP BX
  1463.     POP AX
  1464.     POP SI
  1465.     IRET
  1466.     PAGE;
  1467. ;
  1468. ; Line status interrupt
  1469. ;
  1470. LSI:    MOV DX,LSR[SI]            ; Line status register
  1471.     IN AL,DX            ; Read line status & bump error counts
  1472.     TEST    AL,2            ; OVERRUN ERROR?
  1473.      JZ    LSI1            ; JUMP IF NOT
  1474.     INC    WORD PTR EOVRUN[SI]    ; ELSE BUMP ERROR COUNT
  1475. LSI1:    TEST    AL,4            ; PARITY ERROR?
  1476.      JZ    LSI2            ; JUMP IF NOT
  1477.     INC    WORD PTR EPARITY[SI]    ; ELSE BUMP ERROR COUNT
  1478. LSI2:    TEST    AL,8            ; FRAMING ERROR?
  1479.      JZ    LSI3            ; JUMP IF NOT
  1480.     INC    WORD PTR EFRAME[SI]    ; ELSE BUMP ERROR COUNT
  1481. LSI3:    TEST    AL,16            ; BREAK RECEIVED?
  1482.      JZ    LSI4            ; JUMP IF NOT
  1483.     INC    WORD PTR EBREAK[SI]    ; ELSE BUMP ERROR COUNT
  1484. LSI4:    JMP    REPOLL            ; SEE IF ANY MORE INTERRUPTS
  1485.  
  1486. ;
  1487. ; Modem status interrupt
  1488. ;
  1489. MSI:    MOV DX,MSR[SI]            ; Modem Status Register
  1490.     IN AL,DX            ; Read status & clear interrupt
  1491.     CMP CONNECTION[SI],'D'          ; Direct connection - ignore int
  1492.      JE MSI0            ; Just noise on DSR,CTS pins
  1493.     AND AL,30H            ; Expose CTS and Data Set Ready
  1494.     CMP AL,30H            ; Both on?
  1495.      JE MSI0            ; Yes.    Enable output at TXI
  1496.     XOR AL,AL
  1497.     JMP SHORT MSI1
  1498.  
  1499. MSI0:    MOV AL,1
  1500. MSI1:    MOV SEND_OK[SI],AL        ; Put where TXI and send_com can see
  1501.     MOV DX,IER[SI]            ; Let a TX int happen for thoro chks
  1502.     MOV AL,0FH            ; Line & modem sts, recv, send.
  1503.     OUT DX,AL
  1504.     JMP REPOLL            ; Check for other interrupts
  1505.     PAGE;
  1506. ;
  1507. ; Tranmit interrupt
  1508. ;
  1509. TXI:    CMP SEND_OK[SI],1        ; Harware (CTS & DSR on) OK?
  1510.      JNE TXI9            ; No.  Must wait 'til cable right!
  1511.     MOV CX,1            ; Transfer count for flow ctl
  1512.     CMP URGENT_SEND[SI],1        ; Flow control character to send?
  1513.      JE TXI3            ; Yes.    Always send flow control.
  1514.     CMP PC_OFF[SI],1        ; Flow control (XON/XOFF) OK?
  1515.      JE TXI9            ; Stifled & not urgent. Forget it.
  1516.  
  1517. TXI1:    MOV CL,UART_SILO_LEN[SI]    ; MAX size chunk (1 for simple 8250)
  1518.     ; Too bad there is no "Tranmitter FIFO Full" indication!
  1519.     CMP SIZE_TDATA[SI],CX        ; SEE IF ANY MORE DATA TO SEND
  1520.      JG TXI2            ; UART is the limit
  1521.     MOV CX,SIZE_TDATA[SI]        ; Buffer space limited.  Use that.
  1522. TXI2:     JCXZ TXI9            ; No data, disable TX ints
  1523.  
  1524. TXI3:    CALL TX_CHR            ; Transmit a character
  1525.      LOOP TXI3            ; Keep going 'til silo is full
  1526.     MOV URGENT_SEND[SI],0        ; Tell process level we sent flow ctl
  1527.     JMP    REPOLL
  1528.  
  1529. ; IF NO DATA TO SEND, or can't send, RESET TX INTERRUPT AND RETURN
  1530. TXI9:    MOV DX,IER[SI]
  1531.     MOV AL,0DH            ; Line & modem sts, recv, no send.
  1532.     OUT DX,AL
  1533.     JMP REPOLL
  1534.  
  1535.  
  1536. ; TX_CHR    Internal routine used to actually move a character from
  1537. ;        the transmit buffer to the UART and adjust pointers.
  1538. ;        Called from process and interrupt levels with interrutps
  1539. ;        enabled or disabled.
  1540. ;    Requires: SI pointing at data area for this UART
  1541. ;    Clobbers: AX, BX, DX, ES
  1542. ;    Must preserve: CX  (Caller has count here).
  1543.  
  1544. TX_CHR    PROC NEAR
  1545.     LES BX,TBUFF[SI]        ; Pointer to buffer
  1546.     ADD BX,START_TDATA[SI]        ; ES:BX points to next char to send
  1547.     MOV AL,ES:[BX]            ; Get character from buffer
  1548.     MOV DX,DATREG[SI]        ; I/O address of data register
  1549.     OUT DX,AL            ; Output the character
  1550.     INC BX                ; Bump the head pointer
  1551.     AND BX,S_SIZE-1         ; Ring it
  1552.     MOV START_TDATA[SI],BX        ; Store back in private block
  1553.     DEC SIZE_TDATA[SI]        ; One fewer in buffer now
  1554.     RET
  1555. TX_CHR    ENDP
  1556.     PAGE;
  1557. ;
  1558. ; Receive interrupt
  1559. ;
  1560. RXI:
  1561. RXI0:    MOV DX,LSR[SI]            ; Line Status Register
  1562.     IN AL,DX            ; Read it
  1563.     TEST AL,1            ; Check the RECV DATA READY bit
  1564.      JE RXIX            ; No more data available
  1565.     MOV    DX,DATREG[SI]        ; UART DATA REGISTER
  1566.     IN AL,DX            ; Get data, clear status
  1567.     CMP    XON_XOFF[SI],'E'        ; FLOW CONTROL ENABLED?
  1568.      JNE RXI2            ; No.  Don't check for XON/XOFF
  1569.  
  1570. ; Check each character for possible flow control (XON/XOFF)
  1571.     AND    AL,7FH            ; STRIP PARITY
  1572.     CMP    AL,CONTROL_S        ; STOP COMMAND RECEIVED?
  1573.      JNE RXI1            ; Jump if not. Might be ^Q though.
  1574.     MOV PC_OFF[SI],1        ; Stop output
  1575.     JMP SHORT RXI0            ; Don't store character
  1576.  
  1577. RXI1:    CMP    AL,CONTROL_Q        ; GO COMMAND RECEIVED?
  1578.      JNE RXI2            ; No.  Not a flow control character
  1579.     MOV PC_OFF[SI],0        ; Enable output
  1580.     JMP SHORT RXI0            ; Don't store character
  1581.  
  1582. ; Have a real data byte.  Store if possible.
  1583. RXI2:    CMP    SIZE_RDATA[SI],R_SIZE    ; SEE IF ANY ROOM
  1584.      JL RXI6            ; CONTINUE IF SO
  1585.     INC    WORD PTR EOVFLOW[SI]    ; BUMP OVERFLOW ERROR COUNT
  1586.     JMP SHORT RXIX
  1587.  
  1588. RXI6:    LES BX,RBuff[SI]        ; Receive buffer location
  1589.     ADD BX,END_RDATA[SI]        ; ES:BX points to free space
  1590.     MOV ES:[BX],AL            ; Put character in buffer
  1591.     INC    SIZE_RDATA[SI]        ; GOT ONE MORE CHARACTER
  1592.     MOV BX,END_RDATA[SI]        ; Get the end index
  1593.     INC BX                ; Bump it passed location just used
  1594.     AND BX,R_SIZE-1         ; Ring the pointer
  1595.     MOV    END_RDATA[SI],BX    ; SAVE VALUE
  1596.  
  1597. ; See if we must tell remote host to stop outputting.
  1598.     CMP    XON_XOFF[SI],'E'        ; FLOW CONTROL ENABLED?
  1599.      JNE RXI0            ; No
  1600.     CMP HOST_OFF[SI],1        ; Already told remote to shut up?
  1601.      JE RXI0            ; Yes.    Don't flood him with ^Ss
  1602.     CMP    SIZE_RDATA[SI],R_SIZE/2 ; RECEIVE BUFFER NEARLY FULL?
  1603.      JLE RXIX            ; No.  No need to stifle remote end
  1604.     ; Would like to wait here for URGENT_SEND to go off if it is on.
  1605.     ; But we need to take a TX interrupt for that to happen.
  1606.     MOV    AL,CONTROL_S        ; TURN OFF HOST IF SO
  1607.     CALL    SENDII            ; SEND IMMEDIATELY INTERNAL
  1608.     MOV    HOST_OFF[SI],1        ; HOST IS NOW OFF
  1609. RXIX:    JMP REPOLL
  1610.  
  1611. INT_HNDLR4 ENDP
  1612. INT_HNDLR3 ENDP
  1613. INT_HNDLR2 ENDP
  1614. INT_HNDLR1 ENDP
  1615. COM_TEXT   ENDS
  1616.        END
  1617.